GrowDBH Subroutine

private subroutine GrowDBH(cc, hdmin, hdmax, ws, dws, DBH, height)

update DBH and height tree every new year

Arguments

Type IntentOptional Attributes Name
real(kind=float), intent(in) :: cc

canopy cover

real(kind=float), intent(in) :: hdmin

H/D ratio in carbon partitioning for low density

real(kind=float), intent(in) :: hdmax

H/D ratio in carbon partitioning for high density

real(kind=float), intent(in) :: ws

stem biomass (t/ha)

real(kind=float), intent(in) :: dws

stem biomass increment (t/ha)

real(kind=float), intent(inout) :: DBH
real(kind=float), intent(inout) :: height

Variables

Type Visibility Attributes Name Initial
real(kind=float), public :: dDBH
real(kind=float), public :: dheight
real(kind=float), public :: hdeff

Source Code

SUBROUTINE  GrowDBH &
!
(cc, hdmin, hdmax, ws, dws, DBH, height) 
    
IMPLICIT NONE

!arguments with intent(in):
REAL (KIND = float), INTENT(IN) :: cc !! canopy cover
REAL (KIND = float), INTENT(IN) :: hdmin !! H/D ratio in carbon partitioning for low density
REAL (KIND = float), INTENT(IN) :: hdmax !! H/D ratio in carbon partitioning for high density
REAL (KIND = float), INTENT(IN) :: ws !! stem biomass (t/ha)
REAL (KIND = float), INTENT(IN) :: dws !! stem biomass increment (t/ha)

!arguments with intent inout
REAL (KIND = float), INTENT(INOUT) :: DBH  !diameter at brest height (cm)
REAL (KIND = float), INTENT(INOUT) :: height  !tree height (m)

!local declarations
REAL (KIND = float) :: hdeff
REAL (KIND = float) :: dDBH !DBH increment (cm)
REAL (KIND = float) :: dheight !height increment (m)

!-----------------------------end of declarations------------------------------

IF ( cc <= 0.95) THEN !low density
    hdeff = hdmin + (hdmax - hdmin) * cc
    
ELSE ! high density
    hdeff = hdmax  
END IF

!compute height increment
!dheight = hdeff / (  hdeff / height + 200. / dbh ) * dws / ws

dheight = hdeff / (  hdeff / height) + (200. / dbh ) * dws / ws

!compute DBH increment
dDBH = ( height / hdeff ) + ( 200. / dbh ) * ( dws / ws )


!update dbh and height tree
 DBH = DBH + dDBH
 height = height + dheight
 
 !write(*,*) dheight, hdeff, dws, ws
 !pause

RETURN
END SUBROUTINE GrowDBH